home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / modprolg / mod-prol.lha / Prolog / Examples / search.mod < prev    next >
Text File  |  1992-03-12  |  2KB  |  71 lines

  1. % Taken from Bratko.
  2.  
  3. signature searchsig = 
  4.     sig 
  5.         pred solve/2. 
  6.     end.
  7.  
  8. signature problemsig = 
  9.     sig 
  10.         pred s/2 and goal/1. 
  11.     end.
  12.  
  13. functor dfs(p/problemsig)/searchsig = 
  14.     struct
  15.         structure x = p. 
  16.  
  17.         solve(Node,Solution) :- 
  18.             df([],Node,Solution).
  19.  
  20.         df(Path,Node,[Node|Path]) :- 
  21.             x:goal(Node).
  22.         df(Path,Node,Sol) :- 
  23.             x:s(Node,Node1),
  24.             not member(Node1,Path), % No Cycles!
  25.             df([Node|Path],Node1,Sol).
  26.     end.
  27.  
  28. functor bfs(p/problemsig)/searchsig = 
  29.     struct
  30.         structure x = p. 
  31.  
  32.         solve(Node,Solution) :- 
  33.             bf([[Node]],Solution).
  34.  
  35.         bf([[Node|Path]|_],[Node|Path]) :-
  36.             x:goal(Node).
  37.         bf([[N|Path]|Paths],Solution) :-
  38.             bagof([M,N|Path],
  39.                   (x:s(N,M),not member(M,[N|Path])),
  40.                   Newpaths), % Newpaths = acyclic extensions of [N|Path]
  41.             append(Paths,Newpaths,Paths1), !,
  42.             bf(Paths1,Solution);
  43.             bf(Paths,Solution).   % Case that N has no successors.
  44.     end.
  45.  
  46. structure eightqueens = 
  47.     struct
  48.         goal([_,_,_,_,_,_,_,_]).
  49.  
  50.         s(Queens,[Queen|Queens]) :-
  51.             member(Queen,[1,2,3,4,5,6,7,8]),
  52.         not member(Queen, Queens),
  53.             safe([Queen|Queens]).
  54.  
  55.         safe([]).
  56.         safe([Queen|Others]) :-
  57.             safe(Others),
  58.             noattack(Queen,Others,1).
  59.  
  60.         noattack(_,[],_).
  61.         noattack(Y,[Y1|Ylist],Xdist) :- 
  62.             Y1 - Y =\= Xdist,
  63.             Y - Y1 =\= Xdist, 
  64.             Dist1 is Xdist + 1,
  65.             noattack(Y, Ylist, Dist1).
  66.     end.
  67.     
  68. structure eightbfs = bfs(eightqueens).
  69. structure eightdfs = dfs(eightqueens).
  70.     
  71.